home *** CD-ROM | disk | FTP | other *** search
Oberon Text | 1990-11-07 | 51.0 KB | 997 lines | [.Ob./.Ob*] |
- Syntax24.Scn.Fnt
- Syntax20.Scn.Fnt
- Syntax14.Scn.Fnt
- Syntax10.Scn.Fnt
- Syntax16.Scn.Fnt
- Syntax14i.Scn.Fnt
- Syntax12i.Scn.Fnt
- Syntax12.Scn.Fnt
- MACOBERON REFERENCE MANUAL
- Michael Franz
- SUMMARY
- MacOberon is an implementation of the Oberon system for Apple
- Macintosh II computers, closely resembling the original implementation on
- the personal workstation Ceres. This document supplements the existing
- Oberon documentation and describes those aspects in which MacOberon
- differs from or extends standard Oberon.
- TABLE OF CONTENTS
- 1. Installation and Activation
- 1.1. Files Required by MacOberon
- 1.2. Activation from the Macintosh Finder
- 2. MacOberon Compiler
- 2.0. Introduction
- 2.1. Compiler Options
- 2.2. Module SYSTEM
- 2.3. Data Representation and Alignment
- 2.4. Code Procedures
- 2.5. List of Compiler Errors
- 3. MacOberon Run_Time System
- 3.1. List of MacOberon Run_Time Errors
- 3.2. List of Macintosh File System Errors
- 4. MacOberon Library
- 4.0. Overview
- 4.1. Module Display
- 4.2. Module Input
- 4.3. Modules FileSys and Files
- 4.4. Module System
- 4.5. Module Edit
- 5. Macintosh Toolbox Interfaces
- 5.0. Overview
- 5.1. Macintosh Toolbox Types
- 5.2. Macintosh QuickDraw
- 5.3. Macintosh Window Manager
- 5.4. A Sample Application
- Figures
- Appendix
- 1. INSTALLATION AND ACTIVATION
- 1.1. Files Required by MacOberon
- MacOberon consists of a number of files which have different purposes. All of these
- files have to be contained in a single folder on the Macintosh desktop.
- Most important of all, there is the MacOberon application. This contains the module
- loader and the memory management system, both of which are coded in Assembly
- Language for performance reasons. The MacOberon application must always be
- present for executing code in Oberon modules.
- Besides the MacOberon application, several Oberon object files are supplied. The
- table below displays the basic Oberon modules and their approximate position in the
- module hierarchy. The names of the corresponding object files consist of the module
- names with the suffix ".ObM" (for Object File Motorola 68020) appended to them.
- System Edit
- TextFrames
- MenuViewers
- Oberon Printer
- Texts
- Fonts Viewers
- Modules Reals Files Display Input
- Kernel FileSys
- These modules constitute the standard MacOberon system and their object files are
- required for using the normal Oberon environment on the Macintosh. The MacOberon
- compiler consists of modules which have names starting with either "OP" or "MOP".
- The use of module Fonts further requires the default font file to be present. This file is
- named "Syntax10.Scn.Fnt".
- Several supplementary files are also distributed with MacOberon. There are some
- font files in addition to the default font which can be recognized by a characteristic icon
- (Fig. 1) and the file name suffix ".Scn.Fnt" (for Screen Font). The remaining files are
- either symbol files used by the compiler or text files. Some of these text files contain
- documentation while others, recognizable by file names ending in ".Tool", contain lists
- of commands that may be executed simply by pointing the mouse and pressing a key.
- The file "System.Tool" will automatically be opened at startup.
- MacOberon may be used for the creation of stand_alone application packages that
- use none of the services of the standard modules and therefore do not require them to
- be present. Only the appropriate modules and the MacOberon application are needed
- for using these programs.
- 1.2. Activation from the Macintosh Finder
- MacOberon is started by double_clicking on any Oberon file from the Macintosh Finder
- (or MultiFinder). Unless the Option key is pressed simultaneously, MacOberon will
- then perform its default startup sequence. It will attempt to load the module "Oberon"
- and all modules imported by it. Module Oberon ends its initialization sequence by
- explicitly loading module "System" which causes the remaining standard modules
- (except for "Edit" and "Printer") to be added. Finally, the Main Loop of Oberon is
- entered, polling the mouse and keyboard for input.
- The default loading process may be overruled. By double_clicking on an object file
- while holding down the Option key, a user may designate an Oberon module to be
- loaded directly from the Macintosh Finder. In this case, only those modules that are
- imported by the selected module are processed by the loader. This mechanism
- facilitates the creation of more conventional Macintosh applications that utilize only
- Toolbox interface modules.
- 2. MACOBERON COMPILER
- 2.0. Introduction
- The MacOberon compiler differs from most other compilers for the Macintosh, in that
- it uses a different data alignment and different procedure calling conventions than the
- Macintosh operating system and Toolbox. This improves the execution speed of most
- programs. However, it also demands some extra attention from programmers wishing
- to interface directly to the Macintosh operating system. Chapters 2.3. and 2.4. are for
- the benefit of this category of programmer exclusively and may be passed over by all
- others.
- 2.1. Compiler Options
- The MacOberon compiler accepts a number of options, which may be activated
- independently of each other. The following table lists the available options.
- Selector Function
- s enable generation of a new symbol file
- x disable index checks
- n disable NIL checks of pointer variables
- p disable NIL checks of procedure variables
- t disable type checks
- r enable range checks
- g suppress garbage collection after compiling the current module
- Each file parameter may be followed by a slash ("/") and a list of option selectors.
- Examples:
- Compiler.Compile */n
- Compiler.Compile File1.Mod/sg File2.Mod/sxnt ~
- Unless the /g option is used, the garbage collector will be called between the
- compilation of any two modules. Apart from recycling memory, this will close all files
- that were opened during compilation but are no longer in use, preventing an overflow
- of the file access path table. Exhaustion of available memory occurs far more rarely
- during compilation than a lack of file access paths.
- 2.2. Module SYSTEM
- Module SYSTEM for the Motorola 68020 microprocessor provides some low_level
- operations via procedures which are compiled as in_line code. The interface to the
- MC68020 version of module SYSTEM is identical to that for the National Semiconductor
- 32x32 microprocessor but the semantics of some of the procedures are subtly different,
- reflecting a different machine architecture.
- In the following tables, v stands for a variable, x, y, a and n stand for expressions and
- T for a type.
- 2.2.1. Function Procedures
- Name Argument Types Result Type Function
- ADR(v) any LONGINT address of variable v
- BIT(a, n) a: LONGINT BOOLEAN bit n of Mem[a] (0 <= n <= 7)
- n: integer constant
- CC(n) n: integer constant BOOLEAN CPU condition n (0 <= n < 16)
- FPU condition -n (0 > n > -32)
- LSH(x, n) x, n: integer type LONGINT logical shift (LSL, LSR)
- ROT(x, n) x, n: integer type LONGINT rotation (ROL, ROR)
- VAL(T, x) T, x: any type T x interpreted as of type T
- 2.2.2. Proper Procedures
- Name Argument Types Function
- GET(a, v) a: LONGINT; v: any basic type v := Mem[a]
- PUT(a, x) a: LONGINT; x: any basic type Mem[a] := x
- GETREG(n, v) n: integer constant; v: any basic type v := Rn (see explanation below)
- PUTREG(n, x) n: integer constant; x: any basic type Rn := x (see explanation below)
- MOVE(a0, a1, n) a0, a1, n: integer type, n > 0 Mem[a1+i] := Mem[a0+i], i = 0..n-1
- NEW(v, n) v: any pointer type allocate a storage block of n bytes
- n: integer type and assign its address to v
- The register number supplied to SYSTEM.PUTREG and SYSTEM.GETREG is interpreted as
- follows: If v is of a real type and (0 <= n <= 7), then floating point register Fn is used.
- Otherwise, for (0 <= n <= 7) data register Dn is used, and for (8 <= n <= 15) address
- register An-8 is used.
- 2.3. Data Representation and Alignment
- By default, the MacOberon compiler employs a different data layout and different
- calling conventions than the Macintosh operating system and Toolbox. The Toolbox
- conventions are also supported but their use has to be be explicitly activated by special
- compiler hints embedded in the source program. In order to distinguish between the
- two variants, we will in the following refer to procedures and data structures that
- incorporate these compiler hints as "interfacing" and all others as "pure".
- Observance of the Toolbox conventions is only required when calling operating
- system routines directly. Very few programmers will ever need to do this. Instead, most
- of them will prefer to use the standard Oberon libraries or the Toolbox interface modules
- provided. Although these interface modules themselves make use of the Toolbox
- conventions, this is encapsulated within the modules and need not concern their
- clients.
- 2.3.1. Internal Representation of Data Types Under the Two Different Protocols
- Data Type Toolbox Representation Oberon Default Representation
- SHORTINT not used 1 Byte signed
- INTEGER 2 Bytes signed 2 Bytes signed
- LONGINT 4 Bytes signed 4 Bytes signed
- BYTE 2 Bytes (value in low byte) 1 Byte unsigned
- CHAR 2 Bytes (ASCII code in low byte) 1 Byte unsigned
- BOOLEAN 1 Byte (Boolean value in Bit 0) 1 Byte (0H=FALSE, 0FFH=TRUE)
- SET (Pascal SET OF ...) 4 Bytes unsigned ({0}=1H, ...)
- REAL 4 Bytes IEEE single format 4 Bytes IEEE single format
- LONGREAL 8 Bytes IEEE double format 8 Bytes IEEE double format
- Pointer Type 4 Bytes (NIL = 0) 4 Bytes (NIL = 0)
- Procedure Type 4 Bytes 4 Bytes (NIL = 0)
- Oberon uses a different format than the Macintosh Toolbox for representing the data
- types BYTE and CHAR. The Toolbox representation can be simulated by using the data
- type INTEGER. The MacOberon compiler forbids the use of the types BYTE and CHAR for
- parameters in interfacing procedures and for fields of records or elements of arrays that
- are stored in Toolbox representation. In these cases, the variables or fields in question
- have to be declared as INTEGER. The predefined function procedure ORD() may be
- used for obtaining the correct INTEGER equivalents of bytes and characters.
- Toolbox Representation Oberon Default Representation
- Data Alignment type_size modulo 2 type_size modulo 4
- Parameter Alignment word longword
- Record Padding no padding added padded to longword boundary
- Packed Data Structures (Pascal PACKED ...) simulated by programmer
- 2.3.2. Parameters and Function Results of Pure Oberon Procedures
- The following rules apply to parameters and function results of pure procedures:
- 1. All parameters are longword_aligned.
- 2. Function results are returned in registers. REAL and LONGREAL results are
- returned in floating_point register F0, pointer_valued results are returned in
- address register A0 and all other types of result are returned in data register D0.
- 3. For variable parameters, the address of the variable is passed. If the variable
- parameter is a record, an extra parameter describing the dynamic type of the
- record is added.
- 4. For all dynamic array parameters, an additional parameter describing the length
- of the innermost dimension is passed, plus two additional parameters for
- every higher dimension, describing the length of the array in that dimension and
- the compounded size of all smaller dimensions.
- 5. Dynamic array value parameters are copied by the callee. A pointer to the array is
- passed along with the dimension data.
- 2.3.3. Parameters and Function Results of Interfacing Oberon Procedures
- The following rules apply to parameters and function results of interfacing procedures:
- 1. All parameters are word_aligned.
- 2. Function results are returned on the stack. Space for results is reserved by the
- caller before any parameters are passed.
- 3. For variable parameters, the address of the variable is passed.
- 4. REAL and LONGREAL value parameters are converted to the IEEE extended
- precision (96 bit) format by the caller and a pointer to this value is passed to the
- procedure.
- 5. Array and record_typed value parameters are copied by the caller if the size of the
- structure is smaller than 5 bytes. Otherwise, they are copied by the callee and a
- pointer to the structure is passed.
- 6. Dynamic arrays are not supported.
- 2.3.4. Using Interfacing Data Types in MacOberon
- Interfacing Data structures which have an internal layout according to Toolbox
- conventions are marked by a Plus symbol ("+") following one of the reserved words
- ARRAY, POINTER or RECORD.
- Example:
- TYPE Point = RECORD +
- top, left, bottom, right: INTEGER
- END;
- The MacOberon compiler observes the following rules when Toolbox data types are
- used in Oberon programs:
- 1. The fields of interfacing records and elements of interfacing arrays must be
- simple types (excluding CHAR and BYTE) or must themselves be interfacing
- structures. Interfacing records may not extend pure records. On the other hand,
- pure structure may contain interfacing substructures and may extend them.
- 2. Pointers to interfacing structures must be declared as interfacing pointers, i.e.
- with a Plus mark following the POINTER reserved word. These pointers are
- invisible to the garbage collector. Calls to the standard procedure NEW are
- translated into calls of the operating system trap _NewPtr by the compiler. A
- programmer need not call _NewPtr himself or be concerned about the size of the
- data to be allocated. Deallocation is the responsibility of the programmer.
- 3. Type guards applied to interfacing data structures will never fail. Type extension
- may thus be used for simulating variant records.
- 2.4. Code Procedures
- The MacOberon compiler allows for the declaration of in_line code procedures, which
- are especially useful for representing unimplemented processor instructions by which
- Macintosh Toolbox routines are activated. Code procedures are marked by a Minus
- symbol ("-") following the reserved word PROCEDURE. Instead of a procedure body, an
- arbitrary byte sequence (which may be empty) is given after the formal parameter list.
- This byte sequence is inserted in the object code instead of a regular procedure call
- after space has been reserved for function results (if any) and all parameters have been
- pushed onto the stack.
- Example:
- PROCEDURE - EmptyRgn*(rgn: RgnHandle): BOOLEAN 0A8H, 0E2H;
- Code procedures may be exported, in which case the associated byte sequence is
- contained in the symbol file so that it may be included in client modules. Macintosh
- Toolbox calling conventions are observed for code procedures. Only parameters of
- simple types or interfacing types may be passed to them.
- 2.5. List of MacOberon Compiler Errors
- 2.5.1. Incorrect Use of Oberon Language
- 0 undeclared identifier
- 1 multiply defined identifier
- 2 illegal character in number
- 3 illegal character in string
- 4 identifier does not match procedure name
- 5 comment not closed
- 9 "=" expected
- 10 identifier expected
- 12 type definition starts with incorrect symbol
- 13 factor starts with incorrect symbol
- 14 statement starts with incorrect symbol
- 15 declaration followed by incorrect symbol
- 16 MODULE expected
- 17 number expected
- 18 "." missing
- 19 "," missing
- 20 ":" missing
- 22 ")" missing
- 23 "]" missing
- 24 "}" missing
- 25 OF missing
- 26 THEN missing
- 27 DO missing
- 28 TO missing
- 29 "(" missing
- 33 ":=" missing
- 34 "," or OF expected
- 37 identifier expected
- 38 ";" missing
- 40 END missing
- 43 UNTIL missing
- 45 EXIT not within loop statement
- 47 illegally marked identifier
- 48 unsatisfied forward reference
- 49 recursive import not allowed
- 50 expression should be constant
- 51 constant not an integer
- 52 identifier does not denote a type
- 53 identifier does not denote a record type
- 54 result type of procedure is not a basic type
- 55 procedure call of a function
- 56 assignment to non_variable
- 57 pointer not bound to record or array type
- 58 recursive type definition
- 59 illegal open array parameter
- 60 wrong type of case label
- 61 inadmissible type of case label
- 62 case label defined more than once
- 63 index out of bounds
- 64 more actual than formal parameters
- 65 fewer actual than formal parameters
- 66 element types of actual array and formal open array differ
- 67 actual parameter corresponding to open array is not an array
- 69 parameter must be an integer constant
- 73 procedure must have level 0
- 77 object is not a record
- 78 dereferenced object is not a variable
- 79 indexed object is not a variable
- 80 index expression is not an integer
- 81 index out of specified bounds
- 82 indexed variable is not an array
- 83 undefined record field
- 84 dereferenced variable is not a pointer
- 85 guard or test type is not an extension of variable type
- 86 guard or test type is not a pointer
- 87 guarded or tested variable is neither a pointer nor a VAR_parameter record
- 92 operand of IN not an integer, or not a set
- 93 set element type is not an integer
- 94 operand of & is not of type BOOLEAN
- 95 operand of OR is not of type BOOLEAN
- 96 operand not applicable to (unary) +
- 97 operand not applicable to (unary) -
- 98 operand of ~ is not of type BOOLEAN
- 100 incompatible operands of dyadic operator
- 101 operand type inapplicable to *
- 102 operand type inapplicable to /
- 103 operand type inapplicable to DIV
- 104 operand type inapplicable to MOD
- 105 operand type inapplicable to +
- 106 operand type inapplicable to -
- 107 operand type inapplicable to = or #
- 108 operand type inapplicable to relation
- 110 operand is not a type
- 111 operand inapplicable to (this) function
- 112 operand is not a variable
- 113 incompatible assignment
- 114 string too long
- 115 parameter discrepancy between type (or name) of variable (or forward procedure)
- and this procedure
- 116 type of variable (or forward procedure) has more parameters than this procedure
- 117 type of variable (or forward procedure) has fewer parameters than this procedure
- 118 procedure result type of variable (or of forward declaration) differs from result type
- of this procedure
- 119 assigned procedure is not global
- 120 type of expression following IF, WHILE, or UNTIL is not BOOLEAN
- 121 called object is not a procedure (or is an interrupt procedure)
- 122 actual VAR_parameter is not a variable
- 123 type of actual parameter is not identical with that of formal VAR_parameter
- 124 type of result expression differs from that of procedure
- 125 type of case expression is neither INTEGER nor CHAR
- 126 this expression cannot be a type or a procedure
- 127 illegal use of object
- 129 unsatisfied forward procedure
- 130 WITH clause does not specify a variable
- 131 LEN not applied to array
- 132 dimension in LEN too large or negative
- 133 procedure declaration does not match forward declaration
- 150 key inconsistency of imported module
- 151 incorrect symbol file
- 152 symbol file of imported module not found
- 153 object or symbol file not opened (disk full?)
- 155 generation of new symbol file not allowed
- 2.5.2. Limitations of MacOberon Implementation
- 200 not yet implemented
- 201 lower bound of set range greater than higher bound
- 202 set element greater than MAX(SET) or less than 0
- 203 number too large
- 204 product too large
- 205 division by zero
- 206 sum too large
- 207 difference too large
- 208 overflow in arithmetic shift
- 209 case range too large
- 210 code too long
- 211 jump distance too large
- 213 too many cases in case statement
- 214 too many exit statements
- 215 not enough registers: simplify expression
- 216 not enough floating_point registers: simplify expression
- 217 parameter must be an integer constant
- 218 illegal value of parameter (20 <= p < 256)
- 219 illegal value of parameter (0 <= p < 16)
- 220 illegal value of parameter
- 222 too many pointers (either global, or in record)
- 223 too many record types
- 224 too many pointer types
- 225 address of pointer variable too large (move forward in text)
- 226 too many exported procedures
- 227 too many imported modules
- 228 too many exported structures
- 229 too many nested records for import
- 230 too many constants (strings) in module
- 231 too many link table entries (external procedures)
- 232 too many commands in module
- 233 record extension hierarchy too high
- 240 identifier too long
- 241 string too long
- 2.5.3. Macintosh Toolbox Interface Restrictions
- 300 Macintosh Toolbox uses different CHAR and BYTE representation
- 301 field of an interfacing type declared as a pure structure
- 302 field of an interfacing type declared as a pure pointer
- 303 interfacing procedure variables must not have parameters
- 304 code procedures must not accept dynamic array parameters
- 305 code procedures must not accept pure structures as parameters
- 3. MACOBERON RUN_TIME SYSTEM
- 3.1. List of MacOberon Run_Time Errors
- 2 NIL_reference
- 3 address error
- 4 illegal instruction
- 5 division by zero
- 6 invalid index
- 7 range error in conversion
- 13 integer overflow
- 14 floating_point overflow
- 16 invalid case in CASE statement
- 17 function procedure without RETURN statement
- 18 type guard check
- 19 implied type guard check in record assignment
- 20 Macintosh File System error (check OSErr code and consult File System Error table)
- 21 too many files open
- 22 out of heap space
- 30 - 255 Programmed HALT
- 3.2. List of Macintosh File System Errors
- -19 read error
- -20 write error
- -33 directory full
- -34 disk full
- -35 no such volume
- -36 disk I/O error
- -37 bad name
- -38 file not open
- -39 end of file
- -40 tried to position to before start of file
- -41 memory full or file won't fit
- -42 too many files open
- -43 file not found
- -44 disk is write protected
- -45 file is locked
- -46 volume is locked
- -47 file busy
- -48 duplicate file name
- 4. MACOBERON LIBRARY
- 4.0. Overview
- Several enhancements are necessary for the standard Oberon libraries to accommodate
- some of the peculiarities of the Macintosh environment. All of the variables and
- procedures specified in the "Supplementary Definition" modules below are exported in
- addition to those defined in the standard Oberon documentation and should be
- thought of as extending the basic Oberon system.
- 4.1. Module Display
- SUPPLEMENTARY DEFINITION Display;
- window*: LONGINT; (* Identification of Oberon screen emulation window *)
- neutralize*, restore*: PROCEDURE; (* Screen neutralization and restoration, called from Update *)
- (* Emulation of Oberon Screen inside of Macintosh Window *)
- PROCEDURE Show*;
- PROCEDURE Hide*;
- PROCEDURE Update*; (* Should be called on every update event with theEvent.message=Display.window *)
- (* Pattern Definition *)
- PROCEDURE NewPattern*(W, H: INTEGER; VAR image: ARRAY OF BYTE): Pattern;
- PROCEDURE SetPatternGrey*(pat: Pattern; VAR image: ARRAY OF BYTE);
- (* Off_Line Pattern Accumulation for Acceleration of Display Operations *)
- PROCEDURE OpenCache*(X, Y, W, H: INTEGER);
- PROCEDURE AccumulatePat*(pat: LONGINT; X, Y: INTEGER);
- PROCEDURE TransferCache*(mode: INTEGER);
- (* Restore Standard MacOberon Settings when Changed by Command *)
- PROCEDURE ShowStdMenus*;
- PROCEDURE ShowStdArrow*;
- END Display.
- MacOberon's module Display exports the window pointer of the Oberon window as a
- LONGINT variable. Whenever an update event is received with a message field equal to
- this value, the procedure Display.Update should be activated.
- Display.Update itself calls two installed procedures, Display.neutralize and
- Display.restore, for removing selections and other marks and redrawing the contents of
- the Oberon window. The procedures that are installed as a default are defined in
- module Oberon and shown below. Users may choose to substitute them by their own
- procedures if they wish to use module Display but not Oberon in stand_alone
- application packages. Neutralization prior to redrawing is necessary because the
- restore operation is clipped to the intersection of the window contents and the
- Window Manager's update region while some drawing is performed in transfer mode
- "invert".
- PROCEDURE Neutralize;
- VAR M: Oberon.ControlMsg;
- BEGIN
- M.id := neutralize; Viewers.Broadcast(M); Oberon.FadeCursor(Oberon.Pointer)
- END Neutralize;
- PROCEDURE Restore;
- VAR M: Viewers.ViewerMsg;
- BEGIN
- M.id := Viewers.suspend; Viewers.Broadcast(M);
- M.id := Viewers.restore; Viewers.Broadcast(M)
- END Restore;
- The Oberon window may be hidden by a call to Display.Hide and restored by a call to
- Display.Show. It will automatically be made visible in the event of a trap. Commands
- may also change the appearance of the cursor and of menus as they please and
- conveniently restore the regular look by the procedures provided.
- A standard mechanism is provided for defining Patterns. The image passed to the
- procedure Display.NewPattern should be a standard Macintosh bit image in which the
- number of bytes per pixel row is divisible by four. A Macintosh resource editor may be
- used for creating such images and representing them as a series of hexadecimal values.
- For grey_scale patterns which need to be replicated, an optional QuickDraw_Pattern
- representation may be assigned by use of the procedure Display.SetPatternGrey. If such
- an alternative representation has been defined, QuickDraw_Pattern fill procedures are
- used for replication automatically. Otherwise, replication is executed in an explicit
- loop. Below is an example of a Pattern definition.
- grey: Display.Pattern; img: ARRAY 4 OF LONGINT; qdpat: ARRAY 2 OF LONGINT;
- img[0] := 000000000H; img[1] := 022222222H;
- img[2] := 000000000H; img[3] := 088888888H;
- grey := Display.NewPattern(32, 4, img);
- qdpat[0] := 000220088H; qdpat[1] := 000220088H;
- Display.SetPatternGrey(grey, qdpat);
- Furthermore, a pattern cache is supported which may be used for accelerating display
- operations.
- 4.2. Module Input
- SUPPLEMENTARY DEFINITION Input;
- macEvent*: BOOLEAN; (* TRUE if last MouseDown was handled by Input and should be ignored *)
- backgrounder*: PROCEDURE; (* Called repeatedly by MultiFinder while MacOberon is in background *)
- notifySuspend*, notifyResume*: PROCEDURE; (* Multi Finder event signalling *)
- END Input.
- Due to the architecture of the Macintosh system, applications may receive some events
- which relate not to the contents of their windows but to the environment that the
- applications run in. In the case of MacOberon, some of the mouse and keyboard events
- obtained from the operating system are actually directed at desk accessories or relate to
- menu commands and to the layout of windows on the screen. These need to be
- processed at some lower level and not by the emulated Oberon system.
- This is done as a side effect to polling the keyboard in the procedure Input.Available.
- Whenever the procedure Input.Available is called, the Macintosh event queue is
- scanned and all pending keyboard events are accumulated into a simulated keyboard
- buffer. While this is done, other types of events, such as update events, MultiFinder
- suspend/resume events and desk accessory events, are also extracted and processed.
- Since the mouse state is inspected and saved prior to polling the keyboard in the
- main loop of module Oberon, we provide a global flag in module Input which signals if
- the last mouse event has already been handled and should be ignored by the higher
- module. The main loop in Oberon and all other loops with a similar structure need to
- be augmented by the statements printed in boldface below, in order to ensure that all
- special mouse events are passed over.
- LOOP Input.Mouse(keys, X, Y);
- IF Input.Available() > 0 THEN
- ... (* handle character input *) ...
- ELSIF keys # {} THEN
- IF ~Input.macEvent THEN
- REPEAT ... (* let Viewers.This(X, Y) handle tracking *) ... UNTIL keys = {};
- END
- ELSE
- ... (* redisplay mouse if moved or invisible, then execute next Task in Task queue *) ...
- User commands may make free use of the procedure Input.Mouse to poll the state of
- the mouse button and the simulated additional buttons. However, care has to be taken
- when calling Input.Available because it will access the event queue and remove events
- from it. To be on the safe side, user commands that read the event queue directly
- should respond to keyboard events instead of using Input.Available and Input.Read.
- The procedure installed in Input.backgrounder is called repeatedly while the
- MacOberon application is in the background. The default background handler is
- contained in module Oberon and executes all installed Oberon Tasks in a round_robin
- fashion. Arbitrary procedures may be installed in the procedure variables
- Input.notifySuspend and Input.notifyResume which are called when corresponding
- MultiFinder events are detected.
- Module Input also performs some translations of characters received from the
- Macintosh keyboard into their Oberon equivalent. This applies to umlauted and
- accented characters which have different ordinal values in the Macintosh character set
- than in the Oberon character set. The "esszett" key on Macintosh German keyboards is
- mapped into two strokes of the "s" key.
- 4.3. Modules Files and FileSys
- SUPPLEMENTARY DEFINITION Files;
- PROCEDURE ReadNormBytes*(VAR r: Rider; VAR x: ARRAY OF BYTE; n: LONGINT);
- PROCEDURE WriteNormBytes*(VAR r: Rider; VAR x: ARRAY OF BYTE; n: LONGINT);
- PROCEDURE SetType*(f: File; type, creator: LONGINT);
- END Files.
- MacOberon's module Files extends the standard definition by a mechanism for writing
- data in little_endian byte ordering. The effect of these procedures is defined as follows:
- PROCEDURE ReadNormBytes(VAR r: Files.Rider; VAR x: ARRAY OF BYTE; n: LONGINT);
- VAR i: LONGINT;
- BEGIN i := LEN(x);
- WHILE (n > 0) & (i > 0) DO DEC(i); DEC(n); Files.Read(r, x[i]) END
- END ReadNormBytes;
- PROCEDURE WriteNormBytes(VAR r: Files.Rider; VAR x: ARRAY OF BYTE; n: LONGINT);
- VAR i: LONGINT;
- BEGIN i := LEN(x);
- WHILE n > 0 DO DEC(i); DEC(n); Files.Write(r, x[i]) END
- END WriteNormBytes;
- There is also a procedure for setting the Type and Creator properties supported by the
- Macintosh file system.
- A module FileSys is provided, which implements the low_level file access
- mechanism. Module FileSys exports the file creator and file type values employed by
- MacOberon which should be used when changing the type of Oberon files, and a
- procedure Enumerate which allows access to the file directory. The ListProc passed as a
- parameter to this procedure will be called for all files in the Oberon directory whose
- name starts with the given prefix.
- DEFINITION FileSys; (* Low_Level File Interface *)
- CONST
- FntFile*= 2E466E74H; (* '.Fnt' Font File *)
- ObjFile*= 2E4F624DH; (* '.ObM' Object File *)
- RegFile*= 2E4F622EH; (* '.Ob.' Permanent File *)
- TmpFile*= 2E546D70H; (* '.Tmp' Temporary File *)
- Creator*= 2E4F622AH; (* '.Ob*' Created by Oberon *)
- TYPE
- FileName*= RECORD
- l*: SHORTINT; (* File Name Length *)
- str*: ARRAY 31 OF CHAR (* File Name Characters *)
- END;
- ListProc*= PROCEDURE(VAR name: ARRAY OF CHAR;
- type, creator, crdat, moddat, length: LONGINT);
- nofAccPaths*: INTEGER; (* Number of Access Paths in use by Oberon *)
- PROCEDURE Open*(VAR name: FileName; VAR refNum: INTEGER; VAR found: BOOLEAN);
- PROCEDURE Close*(refNum: INTEGER);
- PROCEDURE Read*(refNum: INTEGER; pos, count: LONGINT; VAR buf: FileName);
- PROCEDURE Write*(refNum: INTEGER; pos, count: LONGINT; VAR buf: FileName);
- PROCEDURE GetEOF*(refNum: INTEGER; VAR eof: LONGINT);
- PROCEDURE SetEOF*(refNum: INTEGER; eof: LONGINT);
- PROCEDURE Create*(VAR name: FileName);
- PROCEDURE Delete*(VAR name: FileName; VAR found: BOOLEAN);
- PROCEDURE Rename*(VAR from, to: FileName; VAR found: BOOLEAN);
- PROCEDURE GetDate*(VAR name: FileName; VAR crdat, moddat: LONGINT);
- PROCEDURE SetType*(VAR name: FileName; type, creator: LONGINT);
- PROCEDURE FlushVol*;
- PROCEDURE Enumerate*(VAR prefix: ARRAY OF CHAR; list: ListProc);
- END FileSys.
- 4.4. Module System
- SUPPLEMENTARY DEFINITION System;
- PROCEDURE Version*; (* Display version date of this Oberon Release *)
- PROCEDURE Debug*; (* Call Macintosh Debugger if present *)
- PROCEDURE Quit*; (* Orderly exit to the Finder, identical to the menu command of the same name *)
- END System.
- The Macintosh version of Module System adds a command for displaying the version
- number of MacOberon in the System.Log viewer. There are also two commands for
- calling the system debugger (by use of the "A9FF" trap), if there is one installed, and for
- terminating the Oberon session in an orderly manner, flushing all file buffers and
- removing anonymous files on the way.
- The commands System.ShowCommands and System.State have been modified to
- optionally accept the most recent selection as a parameter. The commands
- System.ShowModules and System.ShowCommands feature a new option "/a" which may
- be used for displaying the addresses of modules and command procedures.
- The command System.Directory accepts a number of options which may be
- activated independently of each other and are listed in the following table.
- Selector Function
- d display file modification date
- s display file size in Bytes
- l disable file type
- a display all files, including files that were not created by Oberon
- ax display only files that are foreign Oberon
- The file parameter can contain wild_cards ("*") and may be followed by a slash ("/")
- and a list of option selectors.
- Examples:
- System.Directory *.Mod/sd
- System.Directory *bero*/ax
- 4.5. Module Edit
- The Edit.Print command has been modified to facilitate printing to a PostScript file
- which may be downloaded to any compatible printer. The file Oberon.Header.ps
- contains macro declarations that are required for printing the output and is prepended
- to any PostScript file generated. Font substitution instructions for translating between
- Oberon and PostScript fonts are defined in this file and may be changed freely. A
- Percent symbol ("%") following the PostScript file name indicates that output should be
- generated in a fixed_width font, ignoring the formatting information in the documents.
- Examples:
- Edit.Print PostScript0 *
- Edit.Print PostScript1 % File1 File2 File3 ~
- 5. MACINTOSH TOOLBOX INTERFACES
- 5.0. Overview
- A skeletal Toolbox interface is provided in source form along with MacOberon. The
- modules provided may simply be augmented as necessary and new ones may be
- created easily when required.
- It is advantageous to employ a module organization that reflects the decomposition
- of the Toolbox into distinct "managers" (i.e. chapters in the Inside Macintosh
- documentation). However, there is a need for a basic module supplying some data
- types which are used throughout the Macintosh Toolbox interface. Only the type
- definitions of this basic module, MacTypes (which should be left unchanged), and
- excerpts of the interfaces to QuickDraw and the Window Manager are listed here. There
- are more such modules on the MacOberon distribution disk.
- The outline of an exemplary Macintosh application written in Oberon concludes
- this chapter.
- 5.1. Macintosh Toolbox Types
- MODULE MacTypes; (* Macintosh Operating System and Toolbox Interface Base Module *)
- TYPE
- UnpackedChar*= INTEGER; (* Macintosh Character Type *)
- PackedChar*= SHORTINT; (* Character Type as Element of PACKED ARRAY *)
- UnpackedByte*= INTEGER; (* Should be Subrange [0..255] of INTEGER *)
- PackedByte*= SHORTINT; (* Byte as Element of PACKED ARRAY *)
- SignedByte*= SHORTINT; (* Any byte in memory *)
- Fixed*= LONGINT; (* Fixed point arithmetic type *)
- Data*= RECORD + END; (* Base Type of Anything *)
- Ptr*= POINTER + TO Data; (* Blind pointer *)
- Anchor*= RECORD + p*: Ptr END; (* Container for master pointer *)
- Handle*= POINTER + TO Anchor; (* Pointer to a master pointer ['s container] *)
- Point*= RECORD + v*, h*: INTEGER END;
- Rect*= RECORD + top*, left*, bottom*, right*: INTEGER END;
- Str255*= ARRAY + 256 OF PackedChar;
- StringPtr*= POINTER + TO Str255;
- StringAnchor*= RECORD + p*: StringPtr END;
- StringHandle*= POINTER + TO StringAnchor;
- END MacTypes.
- MacTypes defines some data types which are used throughout the Toolbox interface.
- Particularly convenient for low_level Macintosh programming is the empty record type
- "Data" and and its associated pointer type "Ptr". It can be used for correctly
- dereferencing pointers or handles to "raw" data. We may declare extensions of "Data"
- for each data structure in memory that we wish to access via such pointers. An
- appropriate type guard can then be applied to the pointer type because type guards
- never fail when applied to interfacing types. This mechanism therefore has the same
- effect as type_casting of pointers in Pascal and is also similar syntactically. It is also
- useful for simulating Pascal's variant records in Oberon.
- Example:
- TYPE Peek = RECORD +
- (MacTypes.Data)
- byte: SHORTINT
- MacTypes also illustrates how to simulate the data type "Handle", a pointer to a pointer,
- by the use of an intermediate record which we call "Anchor". A common base type for
- all Anchors is not desirable as it eliminates type checking in places where this might be
- helpful.
- Conversion between the MacTypes.Str255 string format and the zero_terminated
- string format that Oberon uses may be achieved by use of the following two procedures
- which are included in module MacTypes on the distribution disk. Note that the
- Toolbox uses a different representation than Oberon for Characters and Bytes that are
- not elements of arrays.
- PROCEDURE SetStr255(chars: ARRAY OF CHAR; VAR theStr255: MacTypes.Str255);
- VAR i: INTEGER; ch: CHAR;
- BEGIN i := 0;
- REPEAT ch := chars[i]; INC(i); theStr255[i] := SHORT(ORD(ch)) UNTIL (ch = 0X) OR (i=256);
- theStr255[0] := SHORT(i-1)
- END SetStr255;
- PROCEDURE GetStr255(VAR theStr255: MacTypes.Str255; VAR chars: ARRAY OF CHAR);
- VAR n: INTEGER; ch: CHAR;
- BEGIN n := theStr255[0];
- IF LEN(chars) < n THEN n := SHORT(LEN(chars)) END;
- WHILE n > 0 DO ch := CHR(theStr255[n]); DEC(n); chars[n] := ch END
- END GetStr255;
- 5.2. Macintosh QuickDraw
- Module MacQuickDraw presents a possible interface to the built_in graphics routines of
- the Macintosh. It contains examples of in_line procedure declarations and
- demonstrates how to access the global variables of QuickDraw from Oberon. A pointer
- to the end of this global variable block is maintained by the Macintosh operating
- system and stored at the address that the processor's address register A5 points to.
- MODULE MacQuickDraw; (* Excerpt of a Macintosh Toolbox Interface Module *)
- IMPORT
- TY:= MacTypes, SYSTEM;
- CONST
- srcCopy*= 0; srcOr*= 1; srcXor*= 2; srcBic*= 3; ... (* Transfer Modes *)
- TYPE
- Pattern*= ARRAY + 8 OF TY.PackedByte;
- BitMap*= RECORD +
- baseAddr*: TY.Ptr;
- rowBytes*: INTEGER;
- bounds*: TY.Rect
- END;
- Cursor*= RECORD +
- data*, mask*: ARRAY + 16 OF INTEGER;
- hotSpot*: TY.Point
- END;
- GrafPtr*= POINTER + TO GrafPort;
- GrafPort*= RECORD +
- device*: INTEGER;
- ...
- END;
- GlobalsPtr* = POINTER + TO Globals; (* Initialized to 0(A5) - 126 *)
- Globals* = RECORD +
- (TY.Data) (* QD offsets *) (* Oberon offsets *)
- randSeed*: LONGINT; (* -126 *) (* 0 *)
- screenBits*: BitMap; (* -122 *) (* 4 *)
- arrow*: Cursor; (* -108 *) (* 18 *)
- dkGray*, ltGray*, gray*, black*, white*: Pattern; (* -40, ..., -8 *) (* 86, ..., 118 *)
- thePort*: GrafPtr (* 0 *) (* 126 *)
- END;
- globals*: GlobalsPtr;
- PROCEDURE - SetPort*(port: GrafPtr) 0A8H, 073H;
- PROCEDURE - GetPort*(VAR port: GrafPtr) 0A8H, 074H;
- BEGIN
- SYSTEM.GETREG(13, globals);
- SYSTEM.GET(SYSTEM.VAL(LONGINT, globals), globals); (* Mem[ 0(A5) ] *)
- DEC(SYSTEM.VAL(LONGINT, globals), 126)
- END MacQuickDraw.
- 5.3. Macintosh Window Manager
- MODULE MacWindows; (* Excerpt of a Macintosh Toolbox Interface Module *)
- IMPORT
- TY:= MacTypes, QD:= MacQuickDraw;
- CONST
- dialogKind*= 2; userKind*= 8; (* Window Kind *)
- TYPE
- WindowPtr*= POINTER + TO WindowRecord;
- WindowRecord*= RECORD +
- (QD.GrafPort)
- windowKind*: INTEGER;
- visible*, hilited*, goAwayFlag*, spareFlag*: BOOLEAN;
- ...
- END;
- PROCEDURE - ShowWindow*(theWindow: WindowPtr) 0A9H, 015H;
- PROCEDURE - HideWindow*(theWindow: WindowPtr) 0A9H, 016H;
- END MacWindows.
- Module MacWindows contains an example of how type extension may be used for
- simulating variant records. This example shows that in many cases type extension is a
- natural concept and well suited for expressing certain kinds of type association. We
- have declared a WindowRecord as an extension of a QuickDraw.GrafPort, whereas in the
- original Toolbox definition the WindowRecord contains a GrafPort as its first field
- which is an unnatural representation of the interrelationship between the two types.
- 5.4. A Sample Application
- A module SampleApp is partly listed below which exports a command SampleApp.Loop,
- embedded inside of which is an event loop similar to that of typical Macintosh
- Applications.
- Modules such as SampleApp may display private cursors and unique menus which
- can be built directly or read from a resource file. The procedures below demonstrate
- how this is done. MacOberon uses resource numbers greater than 32000 while the
- Operating System reserves all numbers smaller than 128. Resource numbers between
- 128 and 32000 may be assigned freely.
- MODULE SampleApp; (* Sample Macintosh Application Running under MacOberon *)
- IMPORT
- SYSTEM, OberonDisplay:= Display,
- TY:= MacTypes, DL:= MacDialogs, DS:= MacDesk, EM:= MacEvents,
- MN:= MacMenus, QD:= MacQuickDraw, WM:= MacWindows;
- CONST (* Resource ID definitions. *)
- AboutAlert= 128;
- AppleMenu= 128; AboutItem= 1;
- FileMenu= 129; QuitItem= 1;
- EditMenu= 130; (* Undo ;- Cut Copy Paste Clear *)
- SampleMenu= 131; DoItItem= 1;
- terminate: BOOLEAN; (* Return to Oberon on next Loop iteration when TRUE *)
- (* Procedures that perform different actions depending on a window classification *)
- PROCEDURE Close(window: WM.WindowPtr); (* Close window *)
- BEGIN
- IF IsOberonWindow(window) THEN OberonDisplay.Hide
- ELSIF IsDAWindow(window) THEN DS.CloseDeskAcc(window.windowKind)
- ELSIF IsSampleWindow(window) THEN WM.CloseWindow(window)
- END
- END Close;
- PROCEDURE Update(window: WM.WindowPtr); (* Update window contents *)
- BEGIN
- IF IsOberonWindow(window) THEN OberonDisplay.Update
- ELSIF IsSampleWindow(window) THEN
- WM.BeginUpdate(window); ... WM.EndUpdate(window)
- END
- END Update;
- (* Procedures that do something useful and distinguish Sample from other applications *)
- PROCEDURE DoIt*; (* Activated when the user chooses DoIt from the menu *)
- BEGIN
- ...
- END DoIt;
- (* Procedures that are required in all applications in some form *)
- PROCEDURE Terminate; (* Close all windows and set Termination Flag *)
- VAR aWindow: WM.WindowPtr;
- BEGIN terminate := TRUE; aWindow := WM.FrontWindow();
- WHILE aWindow # NIL DO Close(aWindow); aWindow := WM.FrontWindow() END
- END Terminate;
- (* User Input and Command Distribution *)
- PROCEDURE MenuCommand(menuResult: LONGINT);
- VAR menuID, menuItem: INTEGER;
- daName: TY.Str255; daRefNum, itemHit: INTEGER; handledByDA: BOOLEAN;
- BEGIN menuID := SHORT(menuResult DIV 10000H);
- menuItem := SHORT(menuResult MOD 10000H);
- CASE menuID OF
- | MN.NoMenu:
- | AppleMenu:
- IF menuItem = AboutItem THEN itemHit := DL.Alert(AboutAlert, NIL)
- ELSE MN.GetItem(MN.GetMHandle(AppleMenu), menuItem, daName);
- daRefNum := DS.OpenDeskAcc(daName)
- END
- | FileMenu:
- IF menuItem = QuitItem THEN Terminate END
- | EditMenu:
- IF IsDAWindow(WM.FrontWindow()) THEN
- handledByDA := DS.SystemEdit(menuItem-1)
- END
- | SampleMenu:
- IF menuItem = DoItItem THEN DoIt END
- END;
- MN.HiliteMenu(MN.NoMenu)
- END MenuCommand;
- PROCEDURE Loop*(); (* Main Loop, activated as a Command *)
- VAR gotEvent: BOOLEAN; event: EM.EventRecord; window: WM.WindowPtr;
- BEGIN SetupSampleLooks; terminate := FALSE;
- REPEAT gotEvent := EM.WaitNextEvent(EM.everyEvent, event, 0, NIL);
- CASE event.what OF (* Dispatch on event type *)
- | EM.updateEvt:
- Update(SYSTEM.VAL(WM.WindowPtr, event.message))
- | EM.mouseDown:
- CASE WM.FindWindow(event.where, window) OF
- | WM.inMenuBar:
- MenuCommand(MN.MenuSelect(event.where))
- | WM.inContent:
- IF window # WM.FrontWindow() THEN WM.SelectWindow(window) END
- | WM.inDrag:
- WM.DragWindow(window, event.where, QD.globals.screenBits.bounds)
- | WM.inGoAway:
- Close(window)
- ...
- END;
- ...
- END
- UNTIL terminate;
- RestoreOberonLooks
- END Loop;
- END SampleApp.
- The main loop of Oberon automatically reinstates Oberon's cursor shape and menu
- layout if these have inadvertently not been restored by user commands. Consequently,
- commands which change the appearance of cursor and menus, such as the procedures
- SetupSampleLooks and RestoreOberonLooks below, may be executed for testing
- purposes without danger of disrupting the correct functioning of the MacOberon
- application.
- PROCEDURE SetupSampleLooks*;
- VAR resName: MacTypes.Str255; menuBar: MacTypes.Handle;
- BEGIN MacTypes.SetStr255("SampleApp.r", resName);
- theResFile:= RM.OpenResFile(resName);
- menuBar := MN.GetNewMBar(MBarResNo);
- MN.SetMenuBar(menuBar); MN.DrawMenuBar;
- QD.SetCursor(QuickDraw.globals.arrow);
- OberonDisplay.Hide
- END SetupSampleLooks;
- PROCEDURE RestoreOberonLooks*;
- BEGIN RM.CloseResFile(theResFile);
- OberonDisplay.ShowStdMenus; OberonDisplay.ShowStdArrow; OberonDisplay.Show
- END RestoreOberonLooks;
- Macintosh Applications are structured differently from Oberon programs, in that
- windows on the screen are not active objects and don't contain a handler to which
- control can be delegated when an event for the window has arrived. Instead, the main
- loop in such applications has to classify the window and then decide what kind of
- action to perform. In SampleApp we differentiate between the Oberon Display, Desk
- Accessories and the windows opened by SampleApp itself. The corresponding
- classification procedures are shown below.
- PROCEDURE IsOberonWindow(window: WM.WindowPtr): BOOLEAN; (* Shell window? *)
- BEGIN RETURN window=SYSTEM.VAL(WM.WindowPtr, OberonDisplay.window)
- END IsOberonWindow;
- PROCEDURE IsDAWindow(window: WM.WindowPtr): BOOLEAN; (* Desk Accessory window? *)
- BEGIN RETURN (window # NIL) & (window.windowKind < 0)
- END IsDAWindow;
- PROCEDURE IsSampleWindow(window: WM.WindowPtr): BOOLEAN; (* Sample's window? *)
- BEGIN
- RETURN (window # NIL) & ~IsOberonWindow(window) &
- ((window.windowKind >= WM.userKind) OR (window.windowKind = WM.dialogKind))
- END IsSampleWindow;
- Debugging programs such as SampleApp in Oberon is simplified greatly by exporting
- individual functions as commands while the application is being developed (e.g.
- SampleApp.DoIt). The constituents of the application may thus be tested separately
- without the burden of a central loop.
- APPENDIX
- Oberon Symbol Files
- The following tables define the format of Oberon symbol files in EBNF notation.
- Names are sequences of characters (bytes) terminated by 0X. Lower case identifiers
- denote numbers, the length of which (in bytes) is appended to the name.
- SymFile = SFtag ModAnchor {Element}.
- SFtag = 0FAX.
- ModAnchor = MOD key4 name.
- Element = ModAnchor
- | CON Constant
- | (TYPE | HDTYPE) Type
- | (VAR | FLD) Variable
- | (VALPAR | VARPAR) Parameter
- | PLIST {Element} (XPRO | IPRO) Procedure
- | PLIST {Element} CPRO CProcedure
- | PTR PointerType
- | PLIST {Element} PROC ProcType
- | ARR ArrayType
- | DARR DynArrType
- | FLIST {Element} REC RecordType
- | (HDPTR | HDPROC) HiddenFldOff
- | FIX Fixup
- | SYS Flag.
- Constant = (BYTE | BOOL | CHAR | SINT) value1 name
- | INT value2 name
- | (LINT | REAL | SET) value4 name
- | LREAL value8 name
- | STRING name name
- | NIL name.
- Type = ref1 modno1 name.
- Variable = ref1 offset4 name.
- Parameter = ref1 offset2 name.
- Procedure = ref1 procno1 name.
- CProcedure = ref1 len1 {code1} name.
- PointerType = baseRef1 modno1.
- ProcType = resultRef1 modno1.
- ArrayType = elemRef1 modno1 size4 boundAdr2 nofElem4.
- DynArrType = elemRef1 modno1 size4 lenOff2.
- RecordType = baseRef1 modno1 size4 descAdr2.
- HiddenFldOff = offset4.
- Fixup = ptrRef1 baseRef1.
- Flag = ref1 sysflag2.
- Two values for the field sysflag in structure descriptions are defined in the first release of
- MacOberon: A value of zero denotes standard MacOberon structures, whereas a value
- of one indicates data structures that have an internal layout according to Macintosh
- Toolbox conventions.
- CON = 1. FLIST = 16. Predefined References:
- TYPE = 2. FLD = 17.
- HDTYPE = 3. HDPTR = 18. UNDEF = 0.
- VAR = 4. HDPROC = 19. BYTE = 1.
- XPRO = 5. FIX = 20. BOOL = 2.
- IPRO = 6. SYS = 21. CHAR = 3.
- CPRO = 7. MOD = 22. SINT = 4.
- PTR = 8. INT = 5.
- PROC = 9. LINT = 6.
- ARR = 10. REAL = 7.
- DARR = 11. LREAL = 8.
- REC = 12. Boolean Constants: SET = 9.
- PLIST = 13. STRING = 10.
- VALPAR = 14. FALSE = 0X NIL = 11.
- VARPAR = 15. TRUE = 1X NOTYP = 12.
-